home *** CD-ROM | disk | FTP | other *** search
Text File | 1990-07-29 | 56.7 KB | 2,102 lines |
- ;
- ; KISS TNC for the TNC-2 and clones
- ;
- ; k3mc 30 Sep 86 - original version
- ;
- ; 1 Mar 87. Fixed all known bugs. Re-arrange code to allow ROMing (this
- ; means that data areas need to be initialized from the code). Figure out the
- ; Stack Pointer given the amount of available RAM. Include the codes 05 00
- ; and 05 01 to mean full duplex off and full duplex on, respectively.
- ; Clear out all available RAM. Do a "dance" with LEDs when initially booted:
- ; Flash the LED(s) for about 5 seconds such that CON only flashes if you have
- ; 8k RAM, STA only flashes if 16k RAM, and STA and CON flash if 32k RAM.
- ;
- ; 29 Mar 87. Add code to discard BREAK chars, and chars with framing errors.
- ; Fix bug in ib_rca which did not discard null received frames.
- ;
- ; 11 Dec 89. Incorporate code from Jan Schiefer, DL5UE, [44.130.48.9]
- ; Degerlocherstrasse 5, 7000 Stuttgart 70, Federal republic of Germany
- ; to fix the problem with Full-Duplex operation. New version number, v.4
-
-
- FALSE equ 0
- TRUE equ NOT FALSE
-
- .z80
- aseg
- org 100h ;silly stuff for CP/M...
-
-
- ;ROM equ TRUE ;uncomment this line to get ROM code
-
- ROM equ FALSE ;uncomment this line for downloadable code
-
-
- ;Note: Next two equates don't matter unless ROM is True.
-
- HOWIE equ FALSE ;uncomment for ROM version org at 0
-
- ;HOWIE equ TRUE ;uncomment for org at 4800h for inclusion in
- ;Howie's code.
-
- if ROM
- if HOWIE
- .phase 4800h
- I_Register equ 48h
- else
- .phase 0
- I_Register equ 0
- endif; HOWIE
- else
- .phase 8000h
- I_Register equ 80h
- endif; ROM
-
-
- SIO equ 0dch ;actually, only A5 is used for SIO -cs
-
- A_dat equ SIO+0 ;Modem port
- A_ctl equ SIO+1 ;Modem port
-
- B_dat equ SIO+2 ;user serial port
- B_ctl equ SIO+3 ;user serial port
-
- DCD equ 8 ;Bit in RR0, used in Ch A
-
- TBE equ 4 ;TX Buffer Empty bit
- RTS equ 2 ;Request To Send (PTT bit in WR5 of Chan A)
- Framing_Error equ 40h ;Bit in RR1 for async framing error
- Break_Abort equ 80h ;Bit in RR0 for async Break detection
-
- FEND equ 300o ;300 octal
- FESC equ 333o ;333 octal
- TFEND equ 334o ;334 octal
- TFESC equ 335o ;335 octal
-
- ALEDon equ 69h ;bits for WR5 to turn on STA LED
- ALEDoff equ 0e9h ;bits for WR5 to turn off STA LED
-
- ALED equ 80h ;The DTR Bit in Ch A WR5, we will soon remove
- ;previous 2 definitions & use the memory loc.
- ;A_WR5 to hold Ch A WR5's value, because we
- ;need to be aware when we are transmitting!
-
- BLEDon equ 6ah ;bits for WR5 to turn on CON LED
- BLEDoff equ 0eah ;bits for WR5 to turn off CON LED
- BLED equ 80h
-
- N_events equ 3 ;so far, only 3 real-time events
- ; 1 test event left untouched
-
- start:
- jp code_start ;go around this data area
- version:
- defb "v.4 11 Dec 89" ;13 bytes (exactly!) here for version string
-
- defw ib_tbe ;ch B transmitter buffer empty interrupt/user
- defw ib_ext ;ch B ext/status change/user
- defw ib_rca ;ch B received char available/user
- defw ib_special ;ch B special receive condition/user
-
- defw ia_tbe ;ch A transmitter buffer empty interrupt/modem
- defw ia_ext ;ch A ext/status change/modem
- defw ia_rca ;ch A received char available/modem
- defw ia_special ;ch A special receive condition/modem
-
- a_init:
- defb 18h,4,20h,1,1bh,7,7eh,5,0e9h,3,0c9h ;For Modem
- a_size equ $-a_init
-
- b_init:
- defb 18h,4,44h,2,10h,3,0c1h,5,0eah,1,1fh ;For TTY
- b_size equ $-b_init
-
-
- ;This is the data area which gets blasted into RAM upon startup:
- data_init:
-
- ;nbuffers:
- db 0 ;up to 255 buffers
- ;free:
- dw 0 ;address of 1st buffer on free list
-
- ;RX_buf:
- dw 0 ;address of current Receive buffer
- ;RX_head:
- dw 0 ;address of 1st RX buffer
- ;RX_Allocated_Buffer:
- db 0 ;set non-zero if we're in RX state
-
- ;RX_Flushing:
- db 0 ;is non-0 if we ran out of buffer
- ;space and are currently flushing this
- ;frame being received. Used by
- ;ia_rca and reset by ia_ext.
-
-
- ;In_Buffer:
- dw 0 ;addr of current Input buffer
- ;In_Head:
- dw 0 ;addr of 1st Input Buffer
- ;In_Allocated_Buffer:
- db 0 ;is not 0 if we've already alloc'd buf
-
- ;In_State:
- db 1 ;convert back to 1 in v.32 code
-
- ;input state machine state
- ;4 Mar 8: Make it 0 (from 1) becuz
- ;noise on line is first triggering the
- ;code to assume that a frame is coming
- ;from the host..... Comment below was
- ;appropriate before
- ;assume that we've seen an FEND from
- ;(non-existent) "previous" frame. This
- ;means that when we are receiving data
- ;from user, there need be ONLY the
- ;FEND char at the end of a frame, and
- ;not at the beginning (although if a
- ;FEND is at the beginning, it is
- ;ignored.)
-
- ;Out_Started:
- db 0 ;Output not started yet (Logical var)
- ;Out_Head_CBuf:
- dw out_top ;address of buffer to be output rs232
- ;Out_Tail_CBuf:
- dw out_top ;pointer to next free output buffer
- ;Out_Chain_Head:
- dw 0 ;addr of buffer we are now outputting
-
- ;TX_Started:
- db 0 ;non-zero if we've begun TXing chars
- ;TX_Head_CBuf:
- dw TX_Top ;Current active CBuf entry (if active)
- ;TX_Tail_CBuf:
- dw TX_Top ;next free CBuf entry
-
- ;TX_Chain_Head:
- dw 0 ;holds address of the current buffer
- ;chain head that we are transmitting
- ;TX_Outstanding:
- db 0 ;Number of TX CBufs queued up for TX
-
- ;DCD_State:
- db 0 ;is non 0 if DCD LED is on
- ;S_H_State:
- db 1 ;Means we are in Sync/Hunt state
-
- ;these next two are used by the IB_TBE interrupt routine.
- ;ib_esc_mode:
- db 0 ; not in escaped mode
- ;ib_char:
- ds 1 ; next char to send if escaped mode
- ;in_break:
- db 0 ; non-zero if we are in a break detect
- ; sequence on the async port
- ;Full_Duplex:
- db 0 ;not Full Duplex to start
- ;A_WR5:
- db ALEDoff ;state of STA LED & RTS (PTT) line,
- ;mainly... (For Ch A only [modem] )
- ;B_WR5:
- db BLEDoff
-
- data_size equ $-data_init
-
- ;***************************************************************************
- code_start:
- di ;No interrupts for the moment...
-
- ;Init SIO. This is required even if we wanna flash LEDs...
-
- in a,(A_ctl) ;assure we are talking to ch 0
- ld c,A_ctl
- ld b,a_size
- ld hl,a_init
- otir ;init sync (modem) port
-
- ;Init Async port, also to allow flashing LEDs
-
- in a,(B_ctl) ;assure we are talking to ch 0
- ld c,B_ctl
- ld b,b_size
- ld hl,b_init
- otir ;init async port & interrupt vector
-
- ;
- ; Figure out where top of stack is, set stack pointer.
- ; silly TNC-2 does not do complete address decoding for the RAMs if you are
- ; using only the two 8k x 8 chips. Hack to figure out top of memory so we can
- ; set stack pointer. Newer hack to see if we've only got 8k RAM.
-
- ld a,(9fffh) ;top of RAM if only 8K
- cpl
- ld b,a
- ld (9fffh),a ;write one's complement into mem
-
- ld a,(9fffh)
- cp b ;see if it "took"
- jp z,ok_8 ;Yes, we have at least 8k of RAM
-
-
- halt ;else there is no RAM, so stop
-
- ok_8:
- ld a,(0bfffh) ;Top of RAM if 16K
- cpl
- ld b,a
- ld (0bfffh),a ;same one's complement hack
-
- ld a,(0bfffh)
- cp b
- jp z,ok_16 ;we have at least 16k of RAM
-
- ld sp,0a000h
- ld d,0ffh ;blink CON LED
- ld e,0 ;but not STA LED (i.e., we have 8k)
- jp stack_loaded ;else we only have 8k of RAM
- ;because previous compare failed
-
- ;Here if we've got at least 16K RAM
- ok_16:
- ld a,55h ;one value
- ld (0bfffh),a
- ld a,0aah
- ld (0ffffh),a ;other value
-
- ld a,(0bfffh) ;get what should be 55h if 32k
-
- cp 55h
- ld sp,0
- ld de,0ffffh ;blink both CON and STA LEDs (if 32k)
- jr z,stack_loaded ;if is 55h, then we've got 32 K, else 16 k
-
- ld sp,0c000h ;force stack value.
- ld d,0 ;do not blink CON LED if 16k RAM
-
- stack_loaded:
- push de ;DE has logical values which tell us which
- ;LEDs to flash (which we do later...)
- exx
- pop hl ;temp. store this info in other reg set
- exx
-
-
- ;Clear out RAM.
-
- ld hl,0
- add hl,sp ;now HL has value of SP (That is, Top of
- ;Memory + 1)
- dec hl ;Now HL has Top of Memory address
- ld de,free_RAM ;get start of available free RAM
- xor a ;clear carry and set A to 0
- ld (de),a ;first free RAM location is zeroed....
- sbc hl,de ;get into HL # of bytes of free RAM. If we
- ;are in ROM, then all RAM is free, else if we
- ;are running from RAM, the code part is not
- ;free, and this compensates for this.
-
- dec hl ;one fewer bytes for number to move...
- ld b,h
- ld c,l ;get Byte Count into BC
-
- ld h,d
- ld l,e ;get "source" address = Free_RAM
-
- inc de ;set "destination" address = Free_RAM + 1
-
- ldir ;Zero memory.
-
- ;This sequence loads up our data area in RAM:
-
- ld hl,data_init
- ld de,nbuffers
- ld bc,data_size
- ldir
-
-
- ; Set stack size and init free buffer list.
-
- ld hl,0
- add hl,sp ;get value of SP, high memory
- ld de,100 ;50 words for stack
- or a ;clear carry
- sbc hl,de ;now hl has "pseudo top of memory"
- ld de,bottom ;"pseudo bottom of memory"
- or a
- sbc hl,de ;hl now has size of available memory
- rl l ;put MSB into carry
- rl h ;put carry into LSB
- ;now h has number of buffers available
- ld a,h
- ld (nbuffers),a ;save this number in memory
-
- ld hl,bottom ;beginning of buffer space
- ld (free),hl ;now it's also top of free list
- ; init buffer free list
- ld b,a ;get nbuffers (see above)
- dec b ;because last one has 0 as "next"
- ibloop:
- push hl
- ld de,128
- add hl,de ;HL has "next" pointer
- ex de,hl ;DE has "next" pointer
- pop hl ;HL now has pointer to current buffer
-
- ld (hl),e ;low byte of "next" pointer first
- inc hl
- ld (hl),d ;now hi byte
- inc hl
- xor a
- ld (hl),a ;zero out count field
- inc hl
- ld (hl),a ;zero out # of bytes read field
-
- ex de,hl ;HL is now pointer to next buffer
- djnz ibloop ;and init all the available buffers
-
- xor a
- ld (hl),a ;Last "next" address is 0
- inc hl
- ld (hl),a ;ditto
-
- inc hl
- ld (hl),a ;zero out count field
- inc hl
- ld (hl),a ;zero out # of bytes read field
-
- ;init regs for ib_ext interrupt
- exx
- ld bc,0 ;set prev state of SYNC pin,for 1200hz
- ld de,0 ;count of # of interrupts init
- exx
-
- xor a
- ld (RX_Allocated_Buffer),a ;not receiving at this time
-
- ld hl,TXQ_enables
- ld b,N_events
- E_clear:
- ld (hl),a ; Turn off all the enables of all ...
- inc hl ; ... possible events.
- djnz E_clear
-
- ;init the routine addresses in our event table
- ld hl,R_Delay
- ld (TXQ_Addresses + 2*0),hl
- ld hl,R_SlotTime
- ld (TXQ_Addresses + 2*1),hl
- ld hl,R_Tail
- ld (TXQ_Addresses + 2*2),hl
-
-
- ld a,50
- ld (TXdelay),a ; TX delay default is 500 ms
- ld a,64
- ld (Persistence),a ; set default value for Persistence
- ld a,10
- ld (SlotTime),a ; and Slot Time defaults to 100 ms
- ld a,3 ; (should be 11 for 300 baud)
- ld (TailTime),a ; Tail Timer default
-
- ld a,1 ; Init Sync/Hunt bit state
- ld (S_H_State),a
-
- ; Now have the CON and STA LEDs do a "dance".
-
- exx
- push hl
- exx
- pop de ;we saved the logicals telling us which LEDs
- ;to flash when we figured out the stacksize.
- ;This is how we know which LEDs to blink.
-
- ld b,6 ;Do it 6 times (arbitrary as hell, but should
- ;be an even number so that the LEDs are off at
- ;the end of this mess...)
- ld hl,0 ;use HL as downcounter
- dance0:
- ld a,d
- or a
- call nz,CON_Flip
- ld a,e
- or a
- call nz,STA_Flip
- dance1:
- dec hl
- ld a,h
- or l
- jp nz,dance1
-
- djnz dance0 ;do this 6 times (3 "cycles")
-
- ;Previous stuff showed that the download or boot worked properly...
-
-
-
- ;We re-initialize the SIO ports so that we flush garbage chars that may have
- ;come in while we were diddling the LEDs. This is necessary because unless we
- ;do this, then the A channel (modem) get RX overrun (esp if TNC was listening
- ;to noise) and RX overrun is VERY BAD - so bad, in fact, that I turn on both
- ;CON and STA and halt, because this situation should NEVER happen in normal
- ;use. I flush the B (tty) channel in case anything was sent to it in mid-
- ;stream.
-
-
- ;Re-Init SIO.
-
- in a,(A_ctl) ;assure we are talking to ch 0
- ld c,A_ctl
- ld b,a_size
- ld hl,a_init
- otir ;init sync (modem) port
-
- ;Re-Init Async port.
-
- in a,(B_ctl) ;assure we are talking to ch 0
- ld c,B_ctl
- ld b,b_size
- ld hl,b_init
- otir ;init async port & interrupt vector
-
-
- ; Prepare to load hi bits of interrupt vector
-
- ld a,I_Register
- ld i,a ;set interrupt page for mode 2 ints
- im 2
- ei ;let 'em rip!
-
- ;-----------------------------------------------------------------------------
- ; This is the background program.
- ; Note that since everything else is interrupt driven, and saves registers,
- ; this part of the code can use registers & expect values to stay.
-
- Commutator_loop:
- ld a,(TX_outstanding) ;if there are no outstanding TX...
- or a ;...frames, then we don't have to...
- jp z,Scan_Check ;...worry about Transmitter
-
- ; If there are frames to transmit, we may have turned on TXdelay, or we may be
- ; transmitting a frame so check first.
- ; (This bug found late on 30 Sep 86) The cleanest way to do
- ; this is to check if we are keyed up. If so, nothing else to do for now
- ; here. This is the "Last Bug!" Found at 11:59pm EDT on 30 Sep.
-
- ld a,(A_WR5)
- and RTS
- jp nz,Scan_Check ;if TX keyed up, nothing for us to
- ;do here!
-
- ; else we've noticed that we've got some frame(s) to send.
- ; try to keyup TX
-
- ld a,(Full_Duplex)
- or a
- jp nz,Key_Up ;if Full Duplex, then there is no
- ;need to worry about all this silly
- ;slot time and persistence stuff!
-
- ld a,(TXQE_SlotTime) ;get SlotTime timer enable
- or a
- jp nz,Scan_Check ;if we're waiting, keep waiting!
-
- ;check if Carrier Detect is active
- ld a,(DCD_State) ;DCD_State is set in interrupt routine
- or a
- jp nz,Scan_Check ;If carrier active, wait it out
-
- ;So, DCD is inactive; do persistence algorithm
- ld a,r ;grab the Z-80 refresh register
- add a,a ;double;now 0 <= A reg <= 254
- ld b,a ;B holds our "random" number
- ld a,(Persistence)
- sub b ;A reg = Persistence - Random #
- jp c,No_PTT ;if (P-r) < 0 then no PTT now
- ; Note that P=255 means ALWAYS key up
-
- ;OK, so we've won with the random number generator. Keyup TX and start the
- ;TXdelay timer
-
- Key_Up:
- ld a,(TXdelay)
- ld h,0
- ld l,a ;HL is 16-bit value of TXdelay
- ld (TXQT_Delay),hl ;Get timer value into timer slot
- ld a,1
- ld (TXQE_Delay),a ;Enable this event
-
- ld a,5
- di ;we need quite time here.
- out (A_ctl),a ;;;Ready to write into WR5 of Ch A
- ld a,(A_WR5)
- or RTS ;;;Turn on the PTT bit...
- ld (A_WR5),a ;;;...in the memory copy of WR5
- out (A_ctl),a ;;; Keyup transmitter
- ei
- jp Scan_Check ;That's all we do for now, we await
- ;TXdelay event
-
- No_PTT: ;since we lost on Random #, wait SlotTime before trying again
- ld a,(SlotTime)
- ld h,0
- ld l,a ;HL has 16-bit version of SlotTime
- ld (TXQT_SlotTime),hl ;Set up the timer value of this event
- ld a,1
- ld (TXQE_SlotTime),a ;and enable this event
- ; Note that this code does not have to be interrupt protected because we
- ; really don't care if the slot timer is decremented between being loaded
- ; and being enabled.
-
- Scan_Check:
- ld hl,TXQ_enables ; gear up to check timer routines
- ld ix,TXQ_timers
- ld iy,TXQ_addresses
- ld de,2 ;bump ix & iy by twos
- ld b,N_events ;Number of possible events
- scan_top:
- ld a,(hl)
- or a
- jp z,scan_bottom ;if not enabled, check next one
-
- ;else is enabled. Timer expired?
- ld a,(ix+1)
- ld c,a ;save MS byte for possible use later
- or (ix)
- jr z,scan_fire ;fire this if we are at 0 count
-
- ld a,c
- or a ; saves us some time doing it this way
- jp p,scan_bottom ; or fire if we are negative
-
- scan_fire:
- xor a
- ld (hl),a ;disable this event as it fires
- push hl
- ld hl,scan_return ;load up routine return address
- push hl ;save as return address on stack
- ld h,(iy+1)
- ld l,(iy) ;get address of routine to "call"
- jp (hl) ;"call" this routine
-
- scan_return: ;where all routines return
- pop hl ;get original HL back
-
- scan_bottom:
- inc hl ;increment enable table pointer
- add ix,de ;keep timer table pointer in step
- add iy,de ;keep routine table pointer in step
- djnz scan_top ;look at all entries in tables
-
-
- ;Now see if we need to start an output to RS-232 (host) port
- ld a,(out_started)
- or a ;also clears carry (see below)
- jp nz,Commutator_loop ;if output started, nothing to do
-
- ; else we should check to see if we need to start an output
- di
- call CON_off ;;;
- ld hl,(out_head_cbuf) ;;;grab current top of circ buf ptr
- ld de,(out_tail_cbuf) ;;;and where the next free buf ptr is
- ei
- ;interrupt protect the pickup of the
- ;two pointers 3 Feb 87
- or a
- sbc hl,de
- jp z,Commutator_loop ;if the same, nothing to do
-
- ;else we need to start an output
- di ;interrupt protect this section,
- ;although I'm not sure it needs it...
- ;3 Feb 87
- ;note: it should already BE done!
- ld hl,(out_head_cbuf) ;;;get pointer to next cbuf to output
- ld e,(hl)
- inc hl
- ld d,(hl) ;;;DE has pointer to buffer chain
- ld (out_chain_head),de ;;;set in interrupt routine's place
- ld a,1
- ld (out_started),a ;;;yes, output started
-
- call CON_on
- cl_0:
- in a,(B_ctl) ;;;look at RR0
- and TBE ;;;isolate the TBE bit
- jr z,cl_0 ;;;wait for transmitter to get done
-
- ld a,FEND
- out (B_dat),a ;;;send FEND character (start txing)
- ei
-
- jp Commutator_loop ;keep looking for new opportunity
-
- ;*****************************************************************************
- ; Timer-driven Events
- ;*****************************************************************************
-
- ;-----------------------------------------------------------------------------
- R_Delay: ; This routine executes when the TX Delay timer expires.
- push af
- push bc
- push de
- push hl
- di
- call TXnext_CBuf ;gets HL to point to buffer chain, and
- ;sets TX_Chain_Head for the interrupt
- ;routine
- ld a,80h
- out (A_ctl),a ;;; reset TX CRC
- call getchar ;;; getchar needs int. protection
- out (A_dat),a ;;; Ship this char to TX modem
- ld a,1
- ld (TX_Started),a ;;; and, yes Virgina, we've started TX
- ld a,0c0h
- out (A_ctl),a ;;; reset TX underrun/EOM latch
- pop hl
- pop de
- pop bc
- pop af
- ei
- ret
-
- ;-----------------------------------------------------------------------------
-
- R_SlotTime: ;when SlotTime event timer expires, come here.
- ret ; we were just waiting, so nothing
- ; else to do here (!)
-
- ;-----------------------------------------------------------------------------
-
- R_Tail: ;When tail timer times out, turn off the TX
-
- push af
- ld a,5 ;ready to write to WR5 of Ch A
- di ;;;must have atomic use of A_WR5 & SIO
- out (A_ctl),a ;;;Next char to A_ctl goes to WR5
- ld a,(A_WR5) ;;;grab A_WR5
- and NOT RTS ;;;turn off RTS bit there
- ld (A_WR5),a ;;;keep memory copy updated
- out (A_ctl),a ;;;and turn off TX now
- ei
- pop af
- ret
-
- ; include IA.MAC ;Modem interrupt catchers
- ;;;---------------------------------------------------------------------------
- ia_tbe:
- push af
- push hl
- ld a,(TX_Started)
- or a
- jp z,ia_t2 ;;; previous frame finished
-
- ld hl,(TX_Chain_Head)
- call getchar
- ld (TX_Chain_Head),hl ;;; must keep this pointer updated
- jr z,ia_t1 ;;; no more to send
-
- out (A_dat),a ;;; else ship this char out
- ia_t9:
- pop hl
- pop af
- ei
- reti ;;; just return from these interrupts
-
- ia_t1:
- ; halt ;;;if it gets here, halt
- xor a
- ld (TX_Started),a ;;; TX is NOT started
- ld hl,TX_Outstanding ;;; make is so that one fewer frames
- ;;; NOT "(TX_Outstanding)" (!) 29 Sep
- dec (hl) ;;; are outstanding
- ld a,28h
- out (A_ctl),a ;;; reset TX interrupt pending
- jp ia_t9
-
- ;;;previous frame is done, SIO now sending a flag. More?
- ia_t2:
- ld a,(TX_Outstanding)
- or a
- jp nz,ia_t21 ;;;if more to send, go there
-
- ;;; else we're done here, clean up.
- ld a,28h
- out (A_ctl),a ;;; Reset TX interrupt pending
-
- ;start Tail timer event
- ld a,(TailTime) ;;; { bug found 30 Sep. It was:
- ld h,0 ;;; "ld hl,(TailTime)"
- ld l,a ;;; [ouch!] }
- ld (TXQT_Tail),hl ;;; wait for CRC to clear TX
- ld a,1 ;;; 8.33 ms/char at 1200 bps
- ld (TXQE_Tail),a ;;; TailTime value SHOULD be >=2.
- jp ia_t9
-
- ia_t21: ;start up next frame
- call TXnext_CBuf ;;; get the next buffer chain pointer
- ;;; setup HL and TX_Chain_Head
- ld a,80h
- out (A_ctl),a ;;; reset TX CRC generator
- call getchar
- out (A_dat),a ;;;get 1st char of next frame
- ld a,1
- ld (TX_Started),a ;;; TX started again
- ld a,0c0h
- out (A_ctl),a ;;; reset TX underrun/EOM latch
- jp ia_t9
-
- ;;;---------------------------------------------------------------------------
- ;;; Got a character from the SIO RX interrupt, deal with it
- ;;; Extensive mods 3 Feb 87 to be in line with what I now know about SIO...
-
- ia_rca:
- push af
- push hl
-
- ld a,(RX_Allocated_Buffer)
- or a
- jp nz,ia_rc7 ;;; Go there if we are in "receiving" state
-
- ;else we are not yet receiving, so allocate buffer & make us "receiving"
-
- call allocate_buffer ;;; get a new buffer
- ; jp z,ia_rc5 ;;; NO ROOM, flush this frame
-
- ;;; if got a buffer, insert this character.
- ;;; after doing initial buffer setup.
-
- ia_rc6:
- ld (RX_head),hl ;;; save chain head address (1st buffer)
- ld (RX_buf),hl ;;; tuck away addr of our current buffer
- ld a,TRUE
- ld (RX_Allocated_Buffer),a ;;; and mark that we are receiving
-
- xor a
- call putchar ;;; SLIP' frame "type" field here (Always 0)
-
- ia_rc7:
- ld hl,(RX_buf) ;;; load up address of our current RX buffer
- in a,(A_dat) ;;; grab the pending character
- call putchar ;;; and stuff in this particular buffer
- ld (RX_buf),hl ;;; HL might have changed in putchar()
-
- ;;;*** NOTE! There is a problem here! If putchar() has no more room, then
- ;;; we need to flush all frames so far accumulated & go into RX_flushing
- ;;; state !!! 3 Feb 87
-
- ia_rc9:
- pop hl
- pop af
-
- ei
- reti ;;; nothing else to do here
-
-
- ;;; if no room, flush this frame (sigh)
- ;ia_rc5:
- ; ld a,TRUE
- ; ld (RX_flushing),a ;;; we are in the midst of flushing this frame
- ia_rc2:
- ; call STA_on ;;;ddd Note that we are in flushing state
- ; in a,(a_dat)
- ; in a,(a_dat)
- ; in a,(a_dat)
- ; in a,(a_dat) ;;; empty SIO Silo
- ;
- ; jp ia_rc9
-
-
- ;;;---------------------------------------------------------------------------
- ;;; From out point of view, this interrupt is only interesting because it
- ;;; tells us if we're at end of frame.
- ia_special:
- push af
- push hl ;;; regs we'll need
-
- ld a,1
- out (A_ctl),a ;;; ready to read RR1
- in a,(A_ctl) ;;; OK, grab RR1
-
- ;;; First check if RX overrun. This is VERY BAD, so what can we do?
- ;;; Well, we merely treat it as a bad CRC, that is, just flushing the
- ;;; frame. I don't like dropping chars (and it shouldn;t happen very often)
- ;;; but at high speeds, it may occur with 2.5 MHz z80s.
-
- bit 5,a ;;; RX overrun?
- jp nz,ia_sp8 ;;; If a problem, treat as bad CRC
- ;;; That is, flush this frame....
- ;ia_sp0:
- bit 7,a ;;; check state of End of Frame bit
- jp z,ia_sp8 ;;; Else something weird happened - probably
- ;;; RX overrun. In any case, flush this frame.
- ;;; error reset & then exit
- ;;; that is, treat like it was a CRC error
-
- ;;; If End of Frame, check CRC bit for valid.
- ia_sp1:
- bit 6,a ;;; Check CRC error bit
- jp nz,ia_sp8 ;;; If CRC error bit is on, then was CRC error
-
- ;;; First ensure that we indeed have a buffer allocated...
- ld a,(RX_Allocated_Buffer)
- or a
- jp z,ia_sp9 ;;; if no buffer allocated, ignore this.
-
- ;;; Else this was a good frame, and we should ship it out to host
- ;;; Leave the first CRC character at end of buffer chain in the buffer, as
- ;;; getchar() will flush it.
-
- ld hl,(RX_head)
- call out_queue_insert ;;; Shove this buffer string onto
- ;;; output queue
- xor a
- ld (RX_Allocated_Buffer),a ;;; We don't have a buffer allocated
- ;;; for the next frame...
- jp ia_sp9
-
- ;;; get here if there was a bad CRC
- ia_sp8:
- ld a,(RX_Allocated_Buffer) ;;; If we don't have any buffers
- ;;; allocated, then
- or a ;;;8 Feb - SET CONDITION CODES !!!!!!
- jp z,ia_sp9 ;;; we MUST NOT "release" them !!! 10 Sep 86
- ;;; if they are not allocated !!!
- ia_spf:
- xor a
- ld (RX_Allocated_Buffer),a ;;; not receiving if we have bad CRC
- ld hl,(RX_head)
- call free_chain ;;; free up all buffer(s)
-
- ia_sp9:
- ld a,30h ;;; error reset
- out (A_ctl),a
- in a,(A_dat) ;;; Avoid spurious RCA interrupt
-
- ld a,03h ;;; [JS] select WR3
- out (A_ctl),a ;;; [JS]
- ld a,0D9h ;;; [JS] enter hunt mode
- out (A_ctl),a ;;; [JS]
- ld a,1 ;;; [JS]
- ld (S_H_State),a ;;; [JS] store sync/hunt state
-
- pop hl
- pop af
-
- ei
- reti
-
- ;;;---------------------------------------------------------------------------
- ;;; for ext/status interrupts on Modem, get DCD state into memory, and
- ;;; deallocate any spurious buffers (buffer stuff done 30 Sep 86).
- ia_ext:
- push af
- ld a,10h ;;; reset ext/status interrupts
- out (A_ctl),a
- in a,(A_ctl) ;;; grab RR0
- push af ;;; [JS] put it aside
- bit 4,a ;;; [JS] check sync/hunt bit
- jp nz,ia_ex1 ;;; [JS] no need to worry, if not zero
- ld a,(S_H_State) ;;; [JS] it is 0! Did it change?
- or a ;;; [JS]
- jp z,ia_ex9 ;;; [JS] no, this is a DCD- or EOM-interrupt
- ld a,0 ;;; [JS] indeed, it changed!
- ld (S_H_State),a ;;; [JS] next time, we'll know
-
- ld a,(RX_Allocated_Buffer) ;;; if we are not in the
- ;;; receiving state...
- or a ;;; then there are no allocated buffers and...
- jp z,ia_ex9 ;;; we MUST NOT "release" them !!! 10 Sep 86
- ;;; if no buffers allocated !!!
- xor a
- ld (RX_Allocated_Buffer),a ;;; not receiving
- push hl
- ld hl,(RX_head)
- call free_chain ;;; free up all buffer(s)
- pop hl
- jp ia_ex9
- ia_ex1:
- ld a,1 ;;; [JS] Prepare for next frame start
- ld (S_H_State),a ;;; [JS]
- ia_ex9:
- pop af ;;; [JS] get pushed value of RR0
- and DCD
- ld (DCD_State),a ;;;save for TX keyup DCD detect. Is 0 if DCD
- ;;;is not active, or non-zero if it is active.
- pop af
- ei
- reti
-
-
- ; include IB.MAC ;TTY interrupt catchers
-
- ;;;---------------------------------------------------------------------------
- ;;; we get here whenever -cts, -dcd or -sync inputs change, as well as break
- ;;; detection. Since -dcd
- ;;; is always tied to +5 volts, we need only worry about -cts and -sync.
- ;;; -cts is wired to pin 20, DTR, of the RS232 connector, and is supposed to
- ;;; be used for host to TNC handshaking; we ignore this transition (We assume
- ;;; that the host is always ready). We also ignore break detection. We are
- ;;; only interested in -sync transitions, so we can keep time.
- ;;; NOTE! This is the ONLY routine that is allowed to use the other reg set!!
- ;;; deal with break detection...
-
- sync_hunt equ 10h
- ib_ext:
- ex af,af'
- exx ;;; we want the other registers
- ld a,10h
- out (B_ctl),a ;;; reset ext/status interrupts
- in a,(B_ctl) ;;; grab RR0
- ld d,a ;;; Hold it for a moment...
- and sync_hunt ;;; isolate this bit
- jp z,ib_s0
- ;else sync/hunt is a 1
- ld a,c
- or a
- jp z,ib_s1 ;;; go here if state of sync/hunt changed
-
-
- ;;; Here if sync/hunt bit did NOT change - maybe something else did....
- ib_s9:
- ld a,d ;;; retreive RRO from above
- and Break_Abort ;;; Check if we are doing a break/abort thing
- jp z,ib_NBA ;;; There if No break/abort
-
- ;;; Else Break/Abort bit on, note state change...
- ld a,1
- ld (in_break),a ;;; save in mem (probably can use E reg...)
- in a,(B_dat) ;;; clear out any null character from buffer
- jp ib_BOK ;;; Break OK for now...
-
- ib_NBA: ;;;if no break/abort, check if we are in break/abort state.
- ld a,(in_break)
- or a
- jp z,ib_BOK ;;; Nothing going on, Break OK
-
- ;;; Else we were in break mode, and this is the tail end of a break.
- xor a
- ld (in_break),a
- in a,(B_dat) ;;; discard the single extraneous null
- ib_BOK:
- ib_s99:
- ex af,af'
- exx
- ei
- reti ;;; else something else & we don't care
- ib_s0: ;;; sync/hunt is a 0
- ld a,c
- or a
- jp nz,ib_s1a ;;; go here if sync/hunt changed
- jp ib_s9 ;;; else not interested, forget it
-
- ;get here if state of sync/hunt changed
- ib_s1:
- ld c,1
- jp ib_s1b
- ib_s1a: ;;; first fix up C for next tick
- ld c,0
- ib_s1b:
- ;;; Here when we've seen a real "clock tick" & dealt with C reg
- inc b
- ld a,b
- cp 12
- jp nz,ib_s99 ;;; we act on every 12th clock tick...
- ld b,0 ;;; so reload divisor. This give us an
- ;;; effective interrupt rate of 100 Hz
-
- ;;; Decrement all the timers
-
- ld hl,(TXQ_timers+2*0) ;;; Get first timer value, and ...
- dec hl ;;; ... decrement it as required.
- ld (TXQ_timers+2*0),hl
-
- ld hl,(TXQ_timers+2*1) ;;; Get second timer value, and ...
- dec hl ;;; ... decrement it as required.
- ld (TXQ_timers+2*1),hl
-
- ld hl,(TXQ_timers+2*2) ;;; Get third timer value, and ...
- dec hl ;;; ... decrement it as required.
- ld (TXQ_timers+2*2),hl
-
- jp ib_s99
-
-
- ;;;---------------------------------------------------------------------------
- ib_special:
- push af
- ib_sp9: ;;; Normal exit
- ld a,30h ;;; error reset
- out (B_ctl),a
- pop af
- ei
- reti
-
- ;;;---------------------------------------------------------------------------
- ;;; The TX has become empty, shove a new character out
- ib_tbe:
- push af ;;; new char will return in A
- push hl
-
- ld a,(ib_esc_mode)
- or a
- jp z,ib_t1 ;;; not escaped, so go here
- ;;; else we are escaped, so send escaped char
- ld a,(ib_char) ;;; char which follows escape
- or a
- jp z,ib_t2 ;;; special case if at end of frame, clean up
- out (B_dat),a
- xor a
- ld (ib_esc_mode),a ;;; get out of escaped mode
- jp ib_t9 ;;; all for now...
- ib_t1:
- ld hl,(out_chain_head) ;;; we are currently on this buffer, as...
- call getchar ;;; getchar() needs to know
- ld (out_chain_head),hl ;;; maybe HL changed, so save it in case
-
- jp z,ib_tdone ;;; if no more chars, deal with this
- cp FESC
- jp z,ib_t1a ;;; deal with FESC char in data stream
- cp FEND
- jp z,ib_t1b ;;; deal with FEND char in data stream
- ;;; else this char is nothing special, so shove it out
-
- out (B_dat),a ;;; shove it out
- jp ib_t9 ;;; if this is not last char, all for now
-
- ;;; else this is last char, send FEND
- ib_tdone:
- ld a,FEND
- out (B_dat),a
- ld a,1
- ld (ib_esc_mode),a ;;; set special escaped mode by...
- xor a
- ld (ib_char),a ;;;... making escaped char a 0
- jp ib_t9 ;;; all till TX Buffer goes empty again.
-
- ; here if are completely done sending frame
- ib_t2:
- push de ;;; need this for a moment
- ld hl,(out_head_cbuf)
- inc hl
- inc hl
- ld de,out_bottom
- or a
- push hl
- sbc hl,de
- pop hl ;;; this may be the one we want
- pop de
- jp nz,ib_t2a ;;; yes it is!
-
- ld hl,out_top ;;; else, make a circular buffer
- ib_t2a:
- ld (out_head_cbuf),hl ;;; we will work on this one next
- xor a
- ld (out_started),a ;;; not doing outputs anymore
- ld (ib_esc_mode),a ;;; !!! NOT IN ESCAPED MODE ANYMORE !!!
-
- ld a,28h ;;; NEEDED for ASYNC
- out (B_ctl),a ;;; reset TX interrupt pending
-
- ib_t9:
- pop hl
- pop af
- ei
- reti ;;; now get our butts out of here...
-
- ;;; here is FESC in data stream
- ib_t1a:
- out (B_dat),a ;;; Ship FESC character to port
- ld a,TFESC ;;; ready what will be next char
- ib_t1z:
- ld (ib_char),a ;;; set char for next time
- ld a,1
- ld (ib_esc_mode),a ;;; we are in escaped mode
- jp ib_t9 ;;; all for now
-
- ;;; here is FEND in data stream
- ib_t1b:
- ld a,FESC
- out (B_dat),a
- ld a,TFEND
- jp ib_t1z ;;; rest is same as FESC case
-
-
- ;;;---------------------------------------------------------------------------
- ;;; Got a char from the TTY port, deal with it.
-
- ib_rca:
- push af
-
- in a,(B_ctl) ;;; Read RR0; force reg pointer to be 0
- ld a,1
- out (B_ctl),a ;;; ready to read RR1
- in a,(B_ctl) ;;; Grab RR1
- and Framing_Error ;;; Isolate the FE bit
- jp z,ib_Rtop ;;; No Framing Error, so process this char
-
- ;;; Else we have a Framing Error - Ignore this char & flush this frame...
- call STA_off ;;; Off with the LED!
- in a,(B_dat) ;;; Flush erroneous character
- xor a
- ld (In_state),a ;;; Force receiver to look for FEND
- ld a,(In_Allocated_Buffer)
- or a
- jp z,ib_rc9 ;;; If no buffer is allocated, done; Exit.
-
- ;;; Else we were receiving a data SLIP frame, so flush it.
- push hl
- ld hl,(In_head)
- call free_chain ;;; Dump these buffers back to free list
- pop hl
- jp ib_rc9 ;;; And get out of here!
-
- ib_rTop:
- ld a,(In_state) ;;; get our state machine value
- or a
- jr z,ib_r0 ;;; in state 0, waiting for FEND
- cp 1
- jr z,ib_r1 ;;; in state 1, saw FEND
- cp 2
- jp z,ib_r2 ;;; in state 2, data to follow
- cp 3
- jp z,ib_r3 ;;; saw FESC, expecting TFESC or TFEND
- cp 10
- jp z,ib_r10 ;;; Expecting TXdelay
- cp 20
- jp z,ib_r20 ;;; Expecting P value
- cp 30
- jp z,ib_r30 ;;; Expecting SlotTime value
- cp 40
- jp z,ib_r40 ;;; Expecting TailTime value
- cp 50
- jp z,ib_r50 ;;; Expecting Full/Half duplex value
-
- ;else we don't know what happened, ignore it.
- ib_rcjunk:
- in a,(B_dat)
- xor a
- ld (In_State),a ;;;go into In_State 0, FEND hunt
- ib_rc9:
- pop af ;;; throw it away, we don't need junk
- ei
- reti
-
- ;;; Here if we are hunting for FEND character
- ib_r0:
- call STA_off
-
- in a,(B_dat)
- cp FEND
- jp nz,ib_rc9 ;;; if we didn't see an FEND, keep looking
-
- ;;; else is an FEND, change state
- ld a,1
- ld (In_state),a
- jp ib_rc9
-
- ;;; Get here if we've seen FEND character; look for command byte
- ib_r1:
- call STA_off
- in a,(B_dat)
- cp FEND
- jp z,ib_rc9 ;;; Just another FEND, keep looking for cmd
-
- call STA_on ;;;getting valid SLIP; show in STA LED
-
- ;;; Here if we DO NOT have an FEND (expecting command byte)
- or a
- jp z,ib_r1a ;;; 0 command means data will follow
- cp 1
- jp z,ib_r1b ;;; 1 command means TXdelay will follow
- cp 2
- jp z,ib_r1c ;;; 2 command means P(Persistence) will follow
- cp 3
- jp z,ib_r1d ;;; 3 command means Slot Time will follow
- cp 4
- jp z,ib_r1e ;;; 4 command means TailTime to follow
- cp 5
- jp z,ib_r1f ;;; 5 command means Full/Half duplex to come
-
- ;;; Here if we receive bogus command byte, flush rest of frame
-
- call STA_off ;;;bogosity, so turn off STA LED
-
- xor a
- ld (In_state),a ;;; go to state which looks for FEND
- jp ib_rc9
-
- ;;; Data are expected, change state
- ib_r1a:
- ld a,2
- ld (In_state),a
- jp ib_rc9
-
- ;;; TXdelay to follow, change state
- ib_r1b:
- ld a,10
- ld (In_state),a
- jp ib_rc9
-
- ;;; P to follow, change state
- ib_r1c:
- ld a,20
- ld (In_state),a
- jp ib_rc9
-
- ;;; SlotTime to follow, change state
- ib_r1d:
- ld a,30
- ld (In_state),a
- jp ib_rc9
-
- ;;; TailTime to follow, change state
- ib_r1e:
- ld a,40
- ld (In_state),a
- jp ib_rc9
-
-
- ;;; Full/Half Duplex to follow, change state
- ib_r1f:
- ld a,50
- ld (In_state),a
- jp ib_rc9
-
-
- ;;; These bytes are data
- ib_r2:
- in a,(B_dat)
- cp FEND
- jr z,ib_r2b ;;; FEND means to queue this buffer
- push af ;;; Save the char we read on stack for a bit..
-
- ld a,(In_Allocated_Buffer)
- or a
- jp nz,ib_r2c ;;; if we already allocated buffer
-
- push hl
- call allocate_buffer ;;; get our initial buffer to mess with
- jp nz,ib_r22
-
- ;;;else no room, flush this frame
- pop hl ;;; keep stack tidy
- xor a
- ld (In_State),a
- jp ib_rc9
-
- ib_r22:
- ld a,1
- ld (In_Allocated_Buffer),a ;;; make ourselves active
-
- ld (In_buffer),hl
- ld (In_head),hl ;;; save current & head of chain pointers
- pop hl
-
- ib_r2c:
- pop af ;;; Retreive the data char we just got...
- cp FESC
- jr z,ib_r2a ;;; If FESC in data stream, switch state
-
- push hl
- ld hl,(In_buffer)
- call putchar ;;; shove this character into our buffer
- ld (In_buffer),hl ;;; save in case HL changed
- pop hl
- jp ib_rc9 ;;; done so far
-
- ;;; FESC character seen while grabbing data
- ib_r2a:
- ld a,3
- ld (In_state),a ;;; go to this other state
- jp ib_rc9
-
- ;;; FEND character seen while grabbing data
- ib_r2b:
- ld a,(In_Allocated_Buffer)
- or a
- jr z,ib_r2z ;;; No bytes accumulated, so is null frame
-
- ;;; else we must ship this frame to TX
- push hl ;;; This bug found 29 Sep (must save HL !!!)
- ld hl,(In_Buffer)
- call putchar ;;; put a garbage character at the end of
- ;;; last buffer because getchar() will strip
- ;;; it. Hack needed because of RX use of
- ;;; putchar/getchar.
- ld hl,(In_head)
- call TX_queue_insert
- pop hl
- xor a
- ld (In_Allocated_Buffer),a ;;; input no longer active
- ib_r2z: ;;; entry point for null frame
- ld a,1 ;;; Keep as was, FENDs only at end in v.32
- ld (In_state),a ;;; go look for another frame
-
- call STA_off ;;;done getting this frame, turn STA LED off
-
- jp ib_rc9
-
-
- ;;; here if we've seen FESC in data stream
- ib_r3:
- in a,(B_dat)
- cp TFESC
- jr z,ib_r3a
- cp TFEND
- jr z,ib_r3b
-
- ;;; Else we don't know what the hell it is, so ignore & keep collecting bytes
- ld a,2
- ld (In_state),a ;;; go back into "data receiving" state
- jp ib_rc9
-
- ;;; here if we've seen TFESC after an FESC in data stream; write an FESC
- ib_r3a:
- ld a,FESC
- ib_r3z:
- push hl
- ld hl,(In_buffer)
- call putchar
- ld (In_buffer),hl
- pop hl
- ld a,2
- ld (In_state),a ;;; get out of escaped mode
- jp ib_rc9
-
- ;;; Here if we've seen TFEND after FESC in data stream; write FEND
- ib_r3b:
- ld a,FEND
- jp ib_r3z ;;; rest is same as for TFESC case
-
-
- ;;; This character is interpreted as TXdelay
- ib_r10:
- in a,(B_dat)
- ld (TXdelay),a
- xor a
- ld (In_state),a ;;; go back to FEND hunt state
- jp ib_rc9
-
- ;;; This charcter is P, Persistence value
- ib_r20:
- in a,(B_dat)
- ld (Persistence),a
- xor a
- ld (In_state),a ;;; go back to FEND hunt state
- jp ib_rc9
-
- ;;; This character is SlotTime value
- ib_r30:
- in a,(B_dat)
- ld (SlotTime),a
- xor a
- ld (In_state),a ;;; go back to FEND hunt state
- jp ib_rc9
-
-
- ;;; This character is TailTime value
- ib_r40:
- in a,(B_dat)
- ld (TailTime),a
- xor a
- ld (In_state),a ;;; go back to FEND hunt state
- jp ib_rc9
-
-
- ;;; This character is Full/Half Duplex value
- ;;; 0 means Half Duplex, non-zero means Full Duplex
- ib_r50:
- in a,(B_dat)
- ld (Full_Duplex),a
- xor a
- ld (In_state),a ;;; go back to FEND hunt state
- jp ib_rc9
-
- ; include BUFFERS.MAC ;all buffer-related stuff in here
- ;plus all (eventually) variables
- ;
- ; The buffer list is kept from "bottom" to the end of RAM. The format of the
- ; buffers is:
-
- ;+------+--------+-------+---------------------------------------------------+
- ;| next | Nbytes | Nread | data |
- ;+------+--------+-------+---------------------------------------------------+
- ;
- ; 2 bytes 1 byte 1 byte 124 bytes (Total 128 bytes)
-
- ; next Pointer to next buffer on this buffer chain (or 0 if no more)
- ; Nbytes Number of bytes in this buffer that are valid
- ; Nread Number of bytes read from this buffer (used by getchar)
- ; data 124 bytes of data (not all is necessarily valid, see Nbytes field)
- ;
- ; The buffer pool is all here, and as processes need buffer space, it is all
- ; allocated out of this pool. See allocate_buffer and free_buffer code.
-
-
- ;;;---------------------------------------------------------------------------
- ;;; return in HL a pointer to a free buffer. If there are not more buffers,
- ;;; return with Z flag set.
- ;;; destroys no registers except return value HL.
- ;;; IS CALLED FROM AN INTERRUPT ROUTINE, so this operation is atomic.
-
- allocate_buffer:
-
- push bc
- push af
-
- ld hl,(free) ;;;get pointer to head of free list
- ld a,h
- or l
- jp nz,OK_allocate_buffer ;;; assure we're not off the end
-
- ;get here if no more buffers. Return Z set - do not disturb A.
- pop af
- ld b,a ;;; tuck A away for a moment...
- xor a ;;; turn on Z bit
- ld a,b ;;; retreive original A
- pop bc
- ret
-
- OK_allocate_buffer:
-
- xor a
- ld c,(hl) ;;;grab lo byte of next free buffer
- ld (hl),a ;;; clear it out
- inc hl
- ld b,(hl) ;;; "ld bc,(hl)" now hi byte
- ld (hl),a ;;; clear it out, too
- ld (free),bc ;;; update with new free list pointer
-
- dec hl ;;; Now HL is at head of new buffer
-
- pop af
- ld b,a ;;; tuck A away for a moment...
- ld a,1
- or a ;;; Turn Z bit off (i.e., all OK)
- ld a,b ;;; retreive original A
-
- pop bc
- ret
-
- ;;;---------------------------------------------------------------------------
- ;;; free_buffer gets passed a pointer (in HL) to a buffer to be freed. The
- ;;; buffer is placed on the head of the free list. The nbytes & nread fields
- ;;; are made 0 before placing on free list.
- ;;; THIS ROUTINE IS CALLED AT INTERRUPT LEVEL, so results are atomic.
- ;;; no registers are disturbed at all. The FREE pointer is updated, however.
- ;;; 159 T states [ 63.6 usec @ 2.5 MHz ]
-
- free_buffer:
- push af
- push bc ;;;we'll use these
- push hl ;;;this will be new head of free list
-
- ld bc,(free) ;;;get old free head
- ld (hl),c ;;;put on free chain, first low byte...
- inc hl
- ld (hl),b ;;; ...now hi byte
- xor a
- inc hl
- ld (hl),a ;;; zero out nbytes field
- inc hl
- ld (hl),a ;;; and the nread field of new head of free
-
- pop hl ;;;get new head of free list back
- ld (free),hl ;;;and save it in memory where it belongs
-
- pop bc
- pop af
- ret
- ;;; --------------------------------------------------------------------------
- ;;; putchar - HL contains pointer to buffer, A contains the character to put
- ;;; into the buffer. Upon return, char is put into this buffer if ther is
- ;;; room, else another buffer is allocated and HL is updated to point to this
- ;;; new buffer. The new buffer is chained onto the old buffer in this case.
- ;;; The calling routine is responsible for maintaing both the head of a
- ;;; particular buffer chain (if it needs it), and the current buffer being
- ;;; manipulated. THIS ROUTINE IS CALLED AT INTERRUPT LEVEL, so is atomic. No
- ;;; registers disturbed, except that HL may have a new value.
- ;;; 211 T states [ 84.4 usec @ 2.5 MHz ] no new buffer required
- ;;; 338 T states [ 135.2 usec @ 2.5 MHz ] New buffer needed
-
- putchar:
- push bc
- push ix
- push af
- push hl ;;;do it this way for a reason...
-
- pop ix ;;;get buffer pointer into IX
- ld a,(ix+2) ;;;grab nbytes field
- cp 124 ;;;max of 124 chars in a buffer
- call z,putc_need_new_buffer
- ;;; if it takes this call, it returns with a new buffer, with HL pointing to
- ;;; it (as well as IX), and with A reg set to 0.
- ;;; else just plunk into buffer
- inc (ix+2) ;;;one more char will go into this buffer
- ld c,a ;;;get previous nbytes
- xor a
- ld b,a ;;; bc <- nbytes, filled out to 16 bits
- add ix,bc ;;; update ix to point to where char goes
- pop af ;;; retreive the char we want to save
- ld (ix+4),a ;;; save it in this buffer
-
- pop ix
- pop bc
- ret ;;;done for the moment
-
- ;;; 127 T states [ 50.8 usec @ 2.5 MHz ] (really part of prev routine)
- putc_need_new_buffer: ;;;prev buffer filled, get a new one
- push de ;;; working registers
- push hl ;;; save current buffer pointer
- call allocate_buffer ;;; grab a new buffer, addr is in HL
- ex de,hl ;;; "ld de,hl" - get new addr into DE for now
- pop hl
- ld (hl),e ;;; link new buffer onto chain, lo byte first
- inc hl
- ld (hl),d ;;; now hi byte, chaining done
-
- ex de,hl ;;; update HL for orig. calling routine's use
- push hl
- pop ix ;;; upper routine needs ix pointing to new buf
- xor a ;;; and A is nbytes in calling routine, make..
- ;;; zero for a new buffer
- pop de ;;; done with this working register
- ret ;;; all done here, let calling routine finish
-
- ;;; --------------------------------------------------------------------------
- ;;; getchar - grab a character from the buffer pointed at by HL, return in A.
- ;;; if the "nread" field of this buf = "nbytes" then this buffer is exhausted,
- ;;; so follow the chain on to the next buffer & release old buffer. If the
- ;;; next chain is 0, or if the nbytes field is >= nread field, then there are
- ;;; no more bytes. In this case, return with Z bit set; normally return with
- ;;; Z bit reset (That is, non-zero) indicating a valid char is in A. Note
- ;;; that if we need to follow the chain to a new buffer, HL will be updated,
- ;;; too, so that the calling routine needs to deal with this.
- ;;; no registers changed except AF and possibly HL.
- ;;; CALLED AT INTERRUPT LEVEL, so operation is atomic.
- ;;; 212 T states [ 84.8 usec @ 2.5 MHz ] No new buffer needed
- ;;; 493 T states [ 197.2 usec @ 2.5 MHz ] if following chain
-
- getchar:
- push ix ;;; save because is working reg
- push bc ;;; working regs here
-
- push hl
- pop ix ;;; ix points to this buffer
-
- ld a,(ix+3) ;;; grab Nread
- cp (ix+2) ;;; compare with Nbytes
- call z,getc_new_buf ;;; if they are same, this buffer is spent
-
- inc (ix+3) ;;; we are reading one more char, update Nread
- inc a
- cp (ix+2)
- jp nz,getc_pluck_character ;;; if not looking at last character
-
- ;;; else, is the "next" pointer 0?
- push hl
- ld b,a ;;; !!!!! SAVE A REG !!!!!!! 4 Jan 87
- ld a,(hl)
- inc hl
- or (hl)
- ld a,b ;;; !!!! Restore A Reg (Gasp!)
- pop hl
- jr nz,getc_pluck_character
-
- ;;; else next is 0 and we are on last char - flush it & quit
- call free_buffer
- pop bc
- pop ix
- ret ;;; note that Z bit is set (from above)
-
- ;;; else we can just pluck a character out of this buffer
- getc_pluck_character:
- dec a ;;; fix A from above mucking around...
-
- ld c,a ;;; get old Nread into BC
- ld b,0 ;;; ditto
- add ix,bc ;;; fix buffer pointer
- ld a,1
- or a ;;; make Z bit reset
- ld a,(ix+4) ;;; get the desired byte
-
- pop bc
- pop ix
- ret ;;; all for this simple case
-
- ;;; old buffer is spent, get new one (if any)
-
- getc_new_buf:
- push de ;;; need this reg here
- ld e,(hl) ;;; get lo byte of Next pointer
- inc hl
- ld d,(hl) ;;; hi byte of Next pointer (now all in DE)
- dec hl ;;; HL now back to point at spent buffer
- call free_buffer ;;; give the buffer back
-
- ex de,hl ;;; "ld hl,de" - follow chain
- push hl
- pop ix ;;; init new IX (same as HL in this routine)
- xor a ;;; A holds Nread (needed above)
- pop de ;;; release DE from use by this excursion
- ret
-
- ;;; --------------------------------------------------------------------------
- ;;; free_chain - MUST be called from interrupt routine to guarantee
- ;;; atomicity. Takes buffer chain pointed at by HL and returns them to free
- ;;; buffer list
- ;;; 303 T states + (n_on_chain-1)*238 T states
- ;;; [ 121.2 usec + (n_on_chain-1)*95.2 usec ]
-
- free_chain:
- push af
- push de
- push hl ;;; we will muck with these
-
- fc_0:
- ld e,(hl) ;;; get lo part of next buffer pointer
- inc hl
- ld d,(hl) ;;; now hi part of next buffer pointer
- dec hl
- call free_buffer ;;; release this buffer
- ld a,d
- or e
- jp z,fc_9 ;;; if "next" address is 0, we are at end
- ;;; else we've got more on this chain - deal with them.
- ex de,hl ;;; "ld hl,de" - HL points to "next"
- jp fc_0
-
- fc_9:
- pop hl
- pop de
- pop af
- ret
-
- ;;; --------------------------------------------------------------------------
- ;;; out_queue_insert - Places the just-received buffer on the output queue.
- ;;; The address of the RX buffer just received is in HL.
- ;;; The output queue is a circular buffer. The output routine keeps sending
- ;;; out buffers until its out_head_cbuf pointer equals its out_tail_cbuf
- ;;; pointer. The output routine never mucks with the out_tail_cbuf pointer;
- ;;; similarly, this routine never changes the out_head_cbuf pointer. So it
- ;;; is possible to
- ;;; insert new entries into the output circular buffer queue without
- ;;; disturbing the entry which is being sent to the output port.
-
- out_queue_insert:
- push af
- push de
- push hl ;;; use these
-
- ex de,hl ;;; "ld de,hl" - move buffer to link addr
- ld hl,(out_tail_cbuf) ;;; Grab next free location
- ld (hl),e ;;; set lo addr 1st
- inc hl
- ld (hl),d ;;; now hi addr
- inc hl ;;; Now HL points to next free entry in...
- ld de,out_bottom ;;; ...circ buf, unless we're at end
- or a ;;; clear carry
- push hl ;;; (may be be needed address)
- sbc hl,de
- pop hl ;;; get back what we think is good
- jp nz,oqi_0
-
- ld hl,out_top ;;; get here if we're at end of circ buffer.
- oqi_0:
- ld (out_tail_cbuf),hl
- pop hl
- pop de
- pop af ;;; keep clean
- ret
-
-
- ;;;---------------------------------------------------------------------------
- ;;; TX_Queue_Insert - similar to Out_queue_insert, but with different queue.
- ;;; Also, increments the byte TX_Outstanding (which counts the number of
- ;;; frames ready to be dumped to the modem port). This routine, like
- ;;; out_queue_insert, does not need to worry about queue wrap-around because
- ;;; there are more entries in each of these queues than there are buffers
- ;;; available. Yes, I know this is a hack, and wastes some RAM space, but it
- ;;; means I don't have to check for overflows here.
- ;;; The queue is circular, and sometimes I call it a "CBuf" - Circular Buffer
-
- TX_Queue_Insert:
- push af
- push de
- push hl
- ex de,hl ;;; "ld de,hl" - save chain head in DE
- ld hl,(TX_Tail_CBuf) ;;; Next free location in TX CBuf
- ld (hl),e
- inc hl
- ld (hl),d ;;; put this chain into TX Queue
- inc hl ;;; HL is next availble TX Queue ...
- ld de,TX_Bottom ;;; ... unless we are at bottom of ...
- or a ;;; ... the TX Queue
- push hl
- sbc hl,de
- pop hl
- jp nz,TQI_0 ;;; go there if not at buffer bottom
-
- ld hl,TX_Top ;;; else reload with top of queue val
- TQI_0:
- ld (TX_Tail_CBuf),hl ;;; save next free queue slot
- ld hl,TX_Outstanding
- inc (hl) ;;; +1 more frame outstanding now
- pop hl
- pop de
- pop af
- ret
-
- ;-----------------------------------------------------------------------------
- ; Setup HL & TX_Chain_Head for transmission of next chain.
-
- TXnext_CBuf:
- push af
- push de
- ld hl,(TX_Head_CBuf)
- ld e,(hl)
- inc hl
- ld d,(hl) ; DE -> next chain to transmit
- inc hl ; HL MIGHT be next CBuf entry pointer
- push de
- ld de,TX_Bottom
- or a ;clear carry
- push hl ;save what might be correct value
- sbc hl,de
- pop hl
- pop de
- jp nz,TXn_1 ;go there if not at end of circ. buf
-
- ld hl,TX_Top ;else we wrap aroune
- TXn_1:
- ld (TX_Head_CBuf),hl ;save next circ buf pointer in mem
- ex de,hl ;return ptr to next chain to TX in HL
- ld (TX_Chain_Head),hl ;TX RCA routine needs this
- pop de
- pop af
- ret
-
-
- ;-----------------------------------------------------------------------------
- STA_on: ;Turn the STA LED on. ASSUMES that interrupts are disabled!
- push af
- ld a,5
- out (A_ctl),a ;;; ready to write WR5
- ld a,(A_WR5) ;;; get memory copy
- and NOT ALED ;;; set DTR bit to 0 so LED goes on
- out (A_ctl),a ;;; Actually turn on STA LED now...
- ld (A_WR5),a ;;; update memory copy
- pop af
- ret
- ;-----------------------------------------------------------------------------
- STA_off: ;Turn the STA LED off. ASSUMES that interrupts are disabled!
- push af
- ld a,5
- out (A_ctl),a ;;; ready to write WR5
- ld a,(A_WR5) ;;; get memory copy
- or ALED ;;; set DTR bit to 1 so LED goes off
- out (A_ctl),a ;;; Actually turn off STA LED now...
- ld (A_WR5),a ;;; update memory copy
- pop af
- ret
-
- ;These routines MUST be called with interrupts disabled!
- ;-----------------------------------------------------------------------------
- STA_flip:
- push af
- push bc
- in a,(A_ctl) ;;;assure we are talking to ch 0
- ld a,5
- out (A_ctl),a ;;; ready to write WR5
- ld a,(A_WR5) ;;; get memory copy
- ld b,a ;;; save original for a moment...
- and ALED ;;; Check the STA LED bit
- ld a,b ;;; retreive original
- jp z,STA_f0 ;;; bit is a 0, so LED is on, make off
- ;else make it go on (because it is now off)
- and NOT ALED ;;; set DTR bit to 0 so LED goes on
- jp STA_f1
- STA_f0:
- or ALED ;;; set DTR bit to 1 so LED goes off
- STA_f1:
- out (A_ctl),a ;;; Actually turn off STA LED now...
- ld (A_WR5),a ;;; update memory copy
- pop bc
- pop af
- ret
-
- ;-----------------------------------------------------------------------------
- CON_on:
- push af
- ld a,5
- out (B_ctl),a
- ld a,BLEDon
- ld (B_WR5),a ;;; save in mem for flip routine
- out (B_ctl),a
- pop af
- ret
- ;-----------------------------------------------------------------------------
- CON_off:
- push af
- ld a,5
- out (B_ctl),a
- ld a,BLEDoff
- ld (B_WR5),a ;;; save in mem for flip routine
- out (B_ctl),a
- pop af
- ret
- ;-----------------------------------------------------------------------------
- CON_flip:
- push af
- push bc
- in a,(B_ctl) ;;;assure we are talking to ch 0
- ld a,5
- out (B_ctl),a ;;; ready to write WR5
- ld a,(B_WR5) ;;; get memory copy
- ld b,a ;;; save original for a moment...
- and BLED ;;; Check the CON LED bit
- ld a,b ;;; retreive original
- jp z,CON_f0 ;;; bit is a 0, so LED is on, make off
- ;else make it go on (because it is now off)
- and NOT BLED ;;; set DTR bit to 0 so LED goes on
- jp CON_f1
- CON_f0:
- or BLED ;;; set DTR bit to 1 so LED goes off
- CON_f1:
- out (B_ctl),a ;;; Actually turn off CON LED now...
- ld (B_WR5),a ;;; update memory copy
- pop bc
- pop af
- ret
-
-
-
- if ROM
-
- Free_RAM equ 8000h
-
- else
-
- Free_RAM equ $
-
- endif; ROM
-
-
- ;-----------------------------------------------------------------------------
- ; These are the TX real-time routine data structures. They are used for
- ; timing required with TX control. There are 3 actions that must be timed:
- ; 1) TXR_delay TX Delay Timer (for TXDELAY function)
- ; 2) TXR_SlotTime Part of p-persistence backoff
- ; 3) TXR_tail Timer to be sending SYNCs before dropping RTS
-
- ; The data structure can be thought of logically as this:
- ;
- ; +------------------------+
- ; | Routine Enabled (byte) | is 0 if not enabled, non zero if enabled
- ; +------------------------+--------------------------------------+
- ; | Pointer to routine to execute when timer expires (word) |
- ; +---------------------------------------------------------------+
- ; | 16-bit downcounter timer value, in 10s of milliseconds (word) |
- ; +---------------------------------------------------------------+
- ;
- ; The data structure has one entry for each of the 3 timer events. Physically
- ; it is organized as 3 separate lists, one for each of the enables, one for
- ; each of the routine pointers, and one for each of the timer values.
- ;
- ; An interupt routine, running at 10 millisecond ticks, decrements the values
- ; in each of the downcount timer whether a routine is enabled or not. When
- ; downcount value goes to 0 (or negative) then the routine "fires". This
- ; checking for "firing" happens at non-interrupt level in the commutator loop.
- ; With this scheme, the minimum time before firing is 10 milliseconds, and the
- ; maximum time is 327.67 seconds (over 5 minutes). For example, for a
- ; TXDELAY of 600 milliseconds, the timer would get loaded with decimal 60.
- ;
- ; When a routine fires, it gets marked as "disabled", so you'd need to
- ; explicitly re-enable it if this is required
-
- ; Note too that a clock could be easily implemented. If we inserted another
- ; event into our list with a timeout of 100, then every second a routine would
- ; be called. In that routine, we could increment the seconds field (and
- ; possibly minutes, hours, days, years fields) of a Time-of-Day clock. We
- ; would immediately re-activate this timer to get the next tick, etc.
-
-
- TXQ_Enables equ Free_RAM
- ;ds 4 ; 4 bytes for the enables
-
- TXQ_Addresses equ TXQ_Enables+4
- ;ds 8 ; 4 words for the routine pointers
-
- TXQ_Timers equ TXQ_Addresses+8
- ;ds 8 ; 4 words for the routine timers
-
- ; NOTE the last slot in this table is for R_Test routine, which blinks STA LED
- ; IT IS NOT USED NORMALLY, JUST FOR HELPING ME DEBUG THIS!
-
- ; Some equates to save us from doing contorted things when we want to check if
- ; a routine is enabled in places other than the commutator loop, or for
- ; enabling routines, etc.
-
- TXQE_Delay equ TXQ_Enables+0
- TXQE_SlotTime equ TXQ_Enables+1
- TXQE_Tail equ TXQ_Enables+2
-
- ; Same idea, but for the timer values
-
- TXQT_Delay equ TXQ_Timers+0
- TXQT_SlotTime equ TXQ_Timers+2
- TXQT_Tail equ TXQ_Timers+4
-
- ; We don't do this for the routine addresses, since they don't change once
- ; they are initialized.
-
-
- TXdelay equ TXQ_Timers+8
- ;ds 1 ; Transmitter Delay time value
-
- Persistence equ TXdelay+1
- ;ds 1 ; Persistence value
-
- SlotTime equ Persistence+1
- ;ds 1 ; Slot Time value
-
- TailTime equ SlotTime+1
- ;ds 1 ; TX Tail Time value
-
-
- nbuffers equ TailTime+1
- ;db 0 ;up to 255 buffers
-
- free equ nbuffers+1
- ;dw 0 ;address of 1st buffer on free list
-
-
- RX_buf equ free+2
- ;dw 0 ;address of current Receive buffer
-
- RX_head equ RX_buf+2
- ;dw 0 ;address of 1st RX buffer
-
- RX_Allocated_Buffer equ RX_head+2
- ;db 0 ;set non-zero if we're in RX state
-
- RX_Flushing equ RX_Allocated_Buffer+1
- ;db 0 ;is non-0 if we ran out of buffer
- ;space and are currently flushing this
- ;frame being received. Used by
- ;ia_rca and reset by ia_ext.
-
-
- In_Buffer equ RX_Flushing+1
- ;dw 0 ;addr of current Input buffer
-
- In_Head equ In_Buffer+2
- ;dw 0 ;addr of 1st Input Buffer
-
- In_Allocated_Buffer equ In_Head+2
- ;db 0 ;is not 0 if we've already alloc'd buf
-
- In_State equ In_Allocated_Buffer+1
- ;db 1 ;input state machine state
- ;assume that we've seen an FEND from
- ;(non-existent) "previous" frame. This
- ;means that when we are receiving data
- ;from user, there need be ONLY the
- ;FEND char at the end of a frame, and
- ;not at the beginning (although if a
- ;FEND is at the beginning, it is
- ;ignored.)
-
- Out_Started equ In_State+1
- ;db 0 ;Output not started yet (Logical var)
-
- Out_Head_CBuf equ Out_Started+1
- ;dw out_top ;address of buffer to be output rs232
-
- Out_Tail_CBuf equ Out_Head_Cbuf+2
- ;dw out_top ;pointer to next free output buffer
-
- Out_Chain_Head equ Out_Tail_Cbuf+2
- ;dw 0 ;addr of buffer we are now outputting
-
-
- TX_Started equ Out_Chain_Head+2
- ;db 0 ;non-zero if we've begun TXing chars
-
- TX_Head_CBuf equ TX_Started+1
- ;dw TX_Top ;Current active CBuf entry (if active)
-
- TX_Tail_CBuf equ TX_Head_CBuf+2 ; This said "TX_Head_CBuf_2"...sigh
- ;type found 2 Mar 87
-
- ;dw TX_Top ;next free CBuf entry
-
-
-
- TX_Chain_Head equ TX_Tail_Cbuf+2
- ;dw 0 ;holds address of the current buffer
- ;chain head that we are transmitting
-
- TX_Outstanding equ TX_Chain_Head+2
- ;db 0 ;Number of TX CBufs queued up for TX
-
-
- DCD_State equ TX_Outstanding+1
- ;db 0 ;is non 0 if DCD LED is on
-
- S_H_State equ DCD_State+1 ;is 1 if we are in Sync/Hunt state
- ;db 1
-
- ;these next two are used by the IB_TBE interrupt routine.
- ib_esc_mode equ S_H_State+1
- ;db 0 ; not in escaped mode
-
- ib_char equ ib_esc_mode+1
- ;ds 1 ; next char to send if escaped mode
-
- in_break equ ib_char+1 ; non-zero if we are in a break detect
- ;db 0 ; on the async port
-
- Full_Duplex equ in_break+1
- ;db 0 ;not initially Full Duplex
-
- A_WR5 equ Full_Duplex+1
- ;db ALEDoff ;state of STA LED & RTS (PTT) line,
- ;mainly... (For Ch A only [modem] )
-
- B_WR5 equ A_WR5+1
- ;db BLEDoff
-
-
-
- Out_Top equ B_WR5+2 ;"top" of output circular buffer
- ; 255 out buffer chains pending, max
- Out_Bottom equ Out_Top+2*255 ;"bottom" of output circular buffer
-
- TX_Top equ Out_Bottom+2
- TX_Bottom equ TX_Top+2*255
-
-
- Bottom equ TX_Bottom+2 ;end of all code & predefined data
-
-
- ; Notes on nomenclature:
-
- ; out = to TTY port; in = from TTY port
- ; TX = to modem; RX = from modem
- ;
- ; ;;; means that that code executes without interrupts enabled (except
- ; for the initialization code)
- ;
- ;
- ; I have been careful with JR/JP use. I use JP when the jump is likely and
- ; where speed is important. I use JR when the jump is unlikely so that I can
- ; save a few cycles. JP always uses 10 cycles whether it jumps or not, but
- ; JR uses either 7 or 12 T states, no jump/jump, respectively.
-
-
- ; Buffers kept here at end.
- end start
-